home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Libris Britannia 4
/
science library(b).zip
/
science library(b)
/
DDJMAG
/
DDJ9206.ZIP
/
FORTEX.ASC
< prev
next >
Wrap
Text File
|
1992-05-18
|
12KB
|
358 lines
_FORTEX: A Fortran Runtime Executive_
by Harold R. Justice
[LISTING ONE]
c- climain.f -- top-level calling system utilized by FORTEX CLI.
c- The main program calls user routine "dynxrun". For CLI-only, this routine
c- the name is arbitrary. When linked to GUI library, "start" button calls
c- the subroutine "dynxrun", a reserved name that MUST be used with the GUI.
c- Dynetics, Inc. 1000 Explorer Blvd. Huntsville, AL 35806 (205) 922-9230
program climain
integer icntl
100 continue
c-------CLEXEC sends the program to the CLI> prompt
CALL CLEXEC(icntl)
c-------check the return code to see whether the user typed 'stop'
if( icntl.lt. 0 ) then
write(*,*)'Normal exit from program'
stop
endif
c-------call the user program to do computations, etc.
call dynxrun
c-----return to the user CLI> prompt so that we may run again
goto 100
end
[LISTING TWO]
c- monte.f -- bob graves -- (c) 1992, dynetics, inc., huntsville, al
c- name type description
c- ---- ---- -----------
c- dbldat dp array to read line of data from file
c- idat int data counter
c- irun int run counter
c- nmnvec int number of points in shortest run
c- nmxvec int number of points in longest run
c- numrun int number of runs read from file
c- there log boolean file exists (t) or not (f)
c- clrecd sub FORTEX data recording routine
c- dynxrun sub main number cruncher for monte program
c- mcavg sub compute average for all points, all runs
c- mcsig sub compute sigma (std dev) for single point
subroutine dynxrun
c- include file listed in clicom.def for FORTEX dictionary
include 'monte.h'
double precision dbldat(100)
logical there
c- error checking
if( nsigma .lt. 0.0 ) then
write(*,*)'err: nsigma negative: defaults to 3.0'
nsigma = 3.0
endif
c- user may access the file name through FORTEX set/display
inquire( file = fname, exist = there )
if( .not. there ) then
write(*, *) 'file not found : ', fname
return
endif
c- file exists, so open.
open( lfdat, file=fname, form='unformatted', status='old')
c- initialize counters.
idat = 1
irun = 1
c- data read loop reads from a FORTEX "clirrr" type file and
c- presumes that time (independent variable) has been prepared
c- first on the list. other parameters are data (nparm of them)
100 continue
read(lfdat,err=110,end=110) t(idat,irun),(dbldat(i),i=1,nparm)
c- pick out the column of data for analysis
work(idat,irun) = dbldat(ivar)
if( idat .gt. 1 ) then
c- test whether we have entered into another run.
if( t(idat, irun ) .lt. t(idat-1,irun) ) then
c- set the number of data points in the run.
num(irun) = idat - 1
irun = irun + 1
if( irun .gt. 1 ) then
c- already into next run, so copy it to first element of next run
t(1, irun ) = t( idat, irun - 1)
work(1, irun ) = work( idat, irun - 1)
endif
idat = 2
goto 100
endif
endif
idat = idat + 1
goto 100
110 continue
c- close the file in case we run again
close(lfdat)
c- assign the number of data points in the last run.
num(irun) = idat - 1
numrun = irun
c- find the length of the shortest and longest runs.
nmxvec = -1
nmnvec = mxdat
do 300 irun = 1, numrun
nmxvec = max ( num(irun), nmxvec )
nmnvec = min ( num(irun), nmnvec )
300 continue
c- determine data extend or truncate mode: trunc=.t., truncate long runs;
c- trunc=.f., extend all shorter runs to be identical to longest run
if ( trunc) then
numvec = nmnvec
else
numvec = nmxvec
imxrun = 1
c- load shorter runs with longest run data. mechanism drives std dev to 0.0
do 350 irun = 1, numrun
if( nmxvec .eq. num(irun) ) then
imxrun = irun
endif
350 continue
c- assign longest run data to shorter run data.
do 410 idat = nmnvec, nmxvec
do 400 irun = 1, numrun
work(idat, irun ) = work(idat, imxrun )
410 continue
400 continue
endif
c- analysis section. looping for FORTEX output.
c- do average and +/- n sigma computations.
call mcavg( avgvec, numvec, numrun, mxdat, work )
do 450 idat = 1, numvec
avg = avgvec(idat)
time = t(idat,1)
call mcsig( avg, idat, numrun, mxdat, work,
. nsigma, sigpos, signeg, sig )
c- FORTEX data recording in clrecd
CALL CLRECD(idat-1)
450 continue
return
end
subroutine mcsig( avg, idat, nrun, mxdat, work,
. nsigma, ps3, ns3, sig )
c- compute +/- n sigma for data passed in.
save
double precision avg, ps3, ns3, sig, work(mxdat,*), sum
c- initialize.
sum = 0.0
c- loop through points.
do 100 irun = 1, nrun
sum = sum + ( work(idat, irun ) - avg )**2
100 continue
if(nrun .gt. 0) then
sig = sqrt(sum / dble( nrun - 1 ))
else
sig = 0.0
endif
c- compute + and - N sigma vectors.
ps3 = avg + nsigma * sig
ns3 = avg - nsigma * sig
return
end
subroutine mcavg( avg, ndat, nrun, mxdat, work )
c- compute the average of nruns of data.
save
double precision avg(*), work(mxdat,*), sum
c- initialize.
do 110 idat = 1, ndat
sum = 0.0
c- loop the nrun loop.
do 100 irun = 1, nrun
sum = sum + work( idat, irun )
100 continue
c- compute the average for this parameter.
avg( idat ) = sum / dble( nrun )
110 continue
c- return.
return
end
block data mondat
include 'monte.h'
c- initialize through data statements, may also use the monte.setup file
data nsigma /3/
data fname /'monte.dat'/
data nparm /2/
data ivar /2/
end
[LISTING THREE]
c- monte.h / dynetics, inc., huntsville, al
c- name type description
c- ---- ---- -----------
c- mxdat parm maximum number of data elements per run
c- mxrun parm maximum number of runs
c- work dp memory copy of raw data for use in statistics
c- avg dp average for a given time point
c- avgvec dp average vector (keep the averages for std dev calc)
c- signeg dp minus n-sigma value for a given time point
c- sigpos dp plus n-sigma value for a given time point
c- sig dp sigma (std dev) for a given time point
c- nsigma int 1,2,or 3 for the +/- N sigma computation
c- t dp time array
c- time dp time for a given point (independent variable)
c- nparm int number of data columns (not counting time) in file
c- lfdat int logical file number of the data
c- fname char name of the input data file (binary)
c- num int array of number of data points per run
c- ivar int which data column to analyze
c- trunc log whether to truncate to shortest run (T) or extrapolate
parameter( mxdat = 1000 )
parameter( mxrun = 100 )
double precision work( mxdat, mxrun )
double precision avg, avgvec(mxdat), signeg, sigpos, sig
double precision t(mxdat, mxrun ), time
common /monted/ work, avg, avgvec, signeg, sigpos, sig, time, t
integer numvar, nsigma, lfdat, nparm, ivar, num(mxrun)
logical trunc
common /monte/ numvar, lfdat, nsigma, nparm, ivar, num, trunc
character*64 fname
common /montec/ fname
[Example 1: MONTE command file]
echo Setup for MONTE program
set fname='traj.rrr'
set ivar = 2
set lfdat = 30
set nparm = 2
prepar time,avg,sigpos,signeg,sig
display 'prepare'
macro facts
echo File name with trajectory data
display fname
echo Number of data columns
display nparm
echo Column of data to analyze
display ivar
end
macro sig3
echo 3 Sigma (nsigma=3)
set nsigma = 3
end
sig3
macro latdat
echo Analyze the crossrange data
set ivar=2
set trunc=.t.
set fname='../inmonte/clirrr'
set nparm=3 $ "number of data columns in missile simulation clirrr file"
facts
output 'clear'
output time,avg,sigpos,signeg
start
plot
end
macro verdat
echo Analyze the altitude data
set ivar=3
set trunc=.t.
set fname='../inmonte/clirrr'
set nparm=3 $ "number of data columns in missile simulation clirrr file"
facts
output 'clear'
output time,avg,sigpos,signeg
start
plot
end
set nciout=10
s cmd=5
[Example 2: Partial output from example run-time session]
riddler77% DYNET-X (C) 1991 FORTRAN RUN-TIME EXECUTIVE V3.06 DYNETICS, INC.
CLI> read 'monte.setup'
Setup for MONTE program
Prepare List
TIME AVG SIGPOS
SIGNEG SIG
End Prepare List
3 Sigma (nsigma=3)
CLI> "Run program to analyze vertical data"
CLI> display nciout
NCIOUT 10
CLI> "Every 10-th data point will be printed to the screen"
CLI> verdat
Analyze the altitude data
File name with trajectory data
FNAME '../inmonte/clirrr '
Number of data columns
NPARM 3
Column of data to analyze
IVAR 3
TIME 0.00000000 AVG 0.00000000 SIGPOS 0.00000000
SIGNEG 0.00000000
TIME 0.09999999 AVG 18.96214371 SIGPOS 20.76645258
SIGNEG 17.15783483
TIME 0.20000002 AVG 32.36762810 SIGPOS 36.44571089
SIGNEG 28.28954530
.
.
.
TIME 4.80001497 AVG 719.5072083 SIGPOS 784.4273663
SIGNEG 654.5870502
TIME 4.90001726 AVG 738.4712952 SIGPOS 805.1422782
SIGNEG 671.8003122
CLI> "Only output every 100th point"
CLI> set nciout=100
CLI> "Run program to analyze the lateral data"
CLI> latdat
Analyze the crossrange data
File name with trajectory data
FNAME '../inmonte/clirrr '
Number of data columns
NPARM 3
Column of data to analyze
IVAR 2
TIME 0.00000000 AVG 0.00000000 SIGPOS 0.00000000
SIGNEG 0.00000000
TIME 0.99999934 AVG 13.08728914 SIGPOS 15.78440254
SIGNEG 10.39017575
TIME 1.99999845 AVG 25.58025684 SIGPOS 28.22318408
SIGNEG 22.93732961
TIME 2.99999762 AVG 37.22265167 SIGPOS 40.50114335
SIGNEG 33.94416000
TIME 3.99999666 AVG 50.43453903 SIGPOS 54.86466342
SIGNEG 46.00441465
CLI> display nsigma
NSIGMA 3
CLI> "Change sigma level to 2"
CLI> set nsigma = 2
CLI> "Run lateral case again to obtain 2-sigma trajectories"
CLI> "Normally, you would type 'start' to run the program"
CLI> "but we would like to illustrate the repeat command"
CLI> !20
latdat
Analyze the crossrange data
File name with trajectory data
FNAME '../inmonte/clirrr '
Number of data columns
NPARM 3
Column of data to analyze
IVAR 2
TIME 0.00000000 AVG 0.00000000 SIGPOS 0.00000000
SIGNEG 0.00000000
TIME 0.99999934 AVG 13.08728914 SIGPOS 14.88536474
SIGNEG 11.28921355
TIME 1.99999845 AVG 25.58025684 SIGPOS 27.34220833
SIGNEG 23.81830535
TIME 2.99999762 AVG 37.22265167 SIGPOS 39.40831279
SIGNEG 35.03699056
TIME 3.99999666 AVG 50.43453903 SIGPOS 53.38795529
SIGNEG 47.48112278
CLI> stop